home *** CD-ROM | disk | FTP | other *** search
/ Libris Britannia 4 / science library(b).zip / science library(b) / PROGRAMM / ASSEMBLE / 0938.ZIP / 286-2.ASM < prev    next >
Assembly Source File  |  1986-07-11  |  10KB  |  318 lines

  1.     PAGE    ,132
  2.     TITLE    Method 2
  3.     .286C    ; Tell MASM 2.0 about 286 instructions
  4. ;--------------------------------------------------------------:
  5. ;    Sample Program 2                        :
  6. ;                                   :
  7. ; This program switches into Protected Virtual Mode, changes   :
  8. ; the display attribute to reverse video, and returns to Real  :
  9. ; Mode to exit to DOS                           :
  10. ;                                   :
  11. ; Once entered into a file, do the following:               :
  12. ;    MASM SAMPLE2;                           :
  13. ;    LINK SAMPLE2;                           :
  14. ;    EXE2BIN SAMPLE2 SAMPLE2.COM                   :
  15. ;    DEL SAMPLE2.EXE                        :
  16. ;                                   :
  17. ; WARNING: This program will "kill" a PC.  It should only      :
  18. ; be run on an AT.                           :
  19. ;--------------------------------------------------------------:
  20.  
  21. bios_data_seg    SEGMENT at    0040h
  22.         ORG        0067h
  23. io_rom_init    dw ?    ; dword variable in BIOS data segment
  24. io_rom_seg    dw ?    ;  used to store a dword address
  25. bios_data_seg    ENDS
  26.  
  27. descriptor    STRUC
  28. seg_limit    dw    0    ; segment limit (1-65536 bytes)
  29. base_lo_word    dw    0    ; 24 bit physical address
  30. base_hi_byte    db    0    ;    (0 - (16M-1))
  31. access_rights    db    0    ; access rights byte
  32.         dw    0    ; reserved_386
  33. descriptor    ENDS
  34.  
  35. cmos_port    equ 070h
  36. code_seg_access equ 10011011b    ;access rights byte for code seg
  37. data_seg_access equ 10010011b    ;access rights byte for data seg
  38. enable_bit20    equ 11011111b    ;8042 function code to gate A20
  39. port_a        equ 060h    ;8042 port A
  40. shut_cmd    equ 0FEh    ;cmd to 8042: shut down AT
  41. shut_down    equ 00Fh    ;CMOS shut down byte index
  42. status_port    equ 064h    ;8042 status port
  43. virtual_enable    equ 0001h    ;LSB=1: Protected Virtual Mode
  44.  
  45.     SUBTTL    Macro Definitions
  46.     PAGE
  47. ;--------------------------------------------------------------:
  48. ; These mnemonics are not supported in MASM 2.0 therefore      :
  49. ; they are supplied here as MACROS.                   :
  50. ;--------------------------------------------------------------:
  51. lgdt    MACRO    lgdt1
  52.     LOCAL    lgdt2,lgdt3
  53.     db    00Fh
  54. lgdt2    label    byte
  55.     mov    dx,word ptr lgdt1
  56. lgdt3    label    byte
  57.     org    offset lgdt2
  58.     db    001h
  59.     org    offset lgdt3
  60.     ENDM
  61.     page
  62.  
  63. lmsw    MACRO    lmsw1
  64.     LOCAL    lmsw2,lmsw3
  65.     db    00Fh
  66. lmsw2    label    byte
  67.     mov    si,ax
  68. lmsw3    label    byte
  69.     org    offset lmsw2
  70.     db    001h
  71.     org    offset lmsw3
  72.     ENDM
  73.  
  74. jumpfar MACRO    jumpfar1,jumpfar2
  75.     db    0EAh
  76.     dw    (offset jumpfar1)
  77.     dw    jumpfar2
  78.     ENDM
  79.  
  80.     SUBTTL    Program entry point and data area
  81.     PAGE
  82. cseg    SEGMENT para        public        'code'
  83.     ASSUME    cs:cseg
  84.  
  85.     ORG    100h
  86. start:    jmp    short    main
  87.  
  88.     EVEN
  89. gdt        LABEL    word
  90.  
  91. gdt_desc    EQU    (($-gdt)/8)*8 + 0000000000000000b
  92. gdt1    descriptor    <gdt_leng,,,data_seg_access,>
  93. cs_code     EQU    (($-gdt)/8)*8 + 0000000000000000b
  94. gdt2    descriptor    <cseg_leng,,,code_seg_access,>
  95. cs_data     EQU    (($-gdt)/8)*8 + 0000000000000000b
  96. gdt3    descriptor    <cseg_leng,,,data_seg_access,>
  97. ss_desc     EQU    (($-gdt)/8)*8 + 0000000000000000b
  98. gdt4    descriptor    <0FFFFh,,,data_seg_access,>
  99. ds_desc     equ    (($-gdt)/8)*8 + 0000000000000000b
  100. gdt5    descriptor    <0FFFFh,,,data_seg_access,>
  101. es_desc     equ    (($-gdt)/8)*8 + 0000000000000000b
  102. gdt6    descriptor    <0FFFFh,,,data_seg_access,>
  103. gdt_leng    EQU    $-gdt
  104.         PAGE
  105. ;--------------------------------------------------------------:
  106. ; Format of the Segment Selector Component:               :
  107. ;                                       :
  108. ; +--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+           :
  109. ; |            INDEX                 +TI+ RPL +           :
  110. ; +--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+           :
  111. ;                                   :
  112. ; TI = Table Indicator (0=GDT, 1=LDT)                   :
  113. ; RPL = Requested Privelege Level (00 = highest; 11 = Lowest)  :
  114. ;--------------------------------------------------------------:
  115. ; Format of the Global Descriptor Table                :
  116. ;          .-----------+             +---> TI           :
  117. ;          V          |             |++-> RPL           :
  118. ; GDT ==> +---------------+   |             |||           :
  119. ;      |   GDT_DESC      | --+    0000000000000000b           :
  120. ;      +---------------+                       :
  121. ;      |    CS_CODE      |    0000000000001000b           :
  122. ;      +---------------+                       :
  123. ;      |    CS_DATA      |    0000000000010000b           :
  124. ;      +---------------+                       :
  125. ;      |    SS_DESC      |    0000000000011000b           :
  126. ;      +---------------+                       :
  127. ;      |    DS_DESC      |    0000000000100000b           :
  128. ;      +---------------+                       :
  129. ;      |    ES_DESC      |    0000000000101000b           :
  130. ;      +---------------+                       :
  131. ;--------------------------------------------------------------:
  132.  
  133.     SUBTTL    Program Main
  134.     PAGE
  135. ;--------------------------------------------------------------:
  136. ; MAIN                                   :
  137. ;--------------------------------------------------------------:
  138.     ASSUME    ds:cseg
  139. main    PROC                  ;ES=DS=CS
  140.     cld                  ;forward
  141.  
  142.     mov    dx,cs              ;form 24bit address out of
  143.     mov    cx,offset gdt          ;CS:GDT
  144.     call    form_24bit_address
  145.     mov    gdt1.base_lo_word,dx  ;DESC now points to gdt
  146.     mov    gdt1.base_hi_byte,cl
  147.  
  148.     mov    dx,cs              ;form 24bit address out of
  149.     xor    cx,cx              ; CS:0000
  150.     call    form_24bit_address
  151.     mov    gdt2.base_lo_word,dx  ;CS_CODE now points to 
  152.     mov    gdt2.base_hi_byte,cl  ; CSEG as a code segment
  153.     mov    gdt3.base_lo_word,dx  ;CS_DATA now points to 
  154.     mov    gdt3.base_hi_byte,cl  ; CSEG as a data segment
  155.  
  156.     mov    dx,ss              ;form 24bit address out of
  157.     xor    cx,cx              ;SS:0000
  158.     call    form_24bit_address
  159.     mov    gdt4.base_lo_word,dx  ;SS_DESC now points to 
  160.                       ; stack segment
  161.     mov    gdt4.base_hi_byte,cl
  162.  
  163.     lgdt    gdt              ;Load the GDTR
  164.  
  165.     mov    ah,enable_bit20       ;gate address bit 20 on
  166.     call    gate_a20
  167.     or    al,al              ;was the command accepted?
  168.     jz    m_10              ;go if yes
  169.     mov    dx,offset gate_failure    ;print error msg 
  170.     mov    ah,9            ; and terminate
  171.     int    21h
  172.     int    20h
  173.  
  174. gate_failure    db    "Address line A20 failed to Gate open$"
  175.  
  176. m_10:    cli            ;No interrupts
  177.     pushf            ;Simulate INT by pushing Flags,
  178.     push    cs        ; CS,
  179.     mov    ax,offset real    ; and offset of return address.
  180.     push    ax
  181.  
  182.     pusha        ;Now, set up stack the way BIOS block-
  183.     push    es    ; move logic will expect it.
  184.     push    ds    ;On return, this is the way 
  185.             ; the regs will be.
  186.  
  187.     ASSUME    ds:bios_data_seg
  188.     mov    dx,bios_data_seg   ;Place on Stack current SS:SP
  189.     mov    ds,dx
  190.     mov    io_rom_seg,ss
  191.     mov    io_rom_init,sp
  192.  
  193.     mov    al,shut_down       ;Set shutdown byte to 
  194.     out    cmos_port,al       ; shut down code x"09"
  195.     jmp    short    $+2       ;I/O delay
  196.     mov    al,9
  197.     out    cmos_port+1,al
  198.  
  199.     mov    ax,virtual_enable  ;machine status word needed
  200.     lmsw    ax           ; to switch to virtual mode
  201.     jumpfar m_20,cs_code       ;Must purge prefetch queue
  202.  
  203. m_20:    ASSUME    ds:cseg        ;IN VIRTUAL MODE ...
  204.     mov    ax,ss_desc       ;stack segment selector
  205.     mov    ss,ax           ;user's ss+sp 
  206.                    ; is not a descriptor
  207.  
  208.     mov    ax,cs_data
  209.     mov    ds,ax           ;DS = CSEG as data
  210.  
  211.     mov    gdt5.base_lo_word,0000h  ;use 8000 for COLOR
  212.     mov    gdt5.base_hi_byte,0Bh
  213.     mov    gdt6.base_lo_word,0000h
  214.     mov    gdt6.base_hi_byte,0Bh
  215.  
  216.     mov    ax,ds_desc
  217.     mov    ds,ax
  218.     mov    ax,es_desc
  219.     mov    es,ax
  220.     mov    cx,80*25
  221.     xor    si,si
  222.     xor    di,di
  223. m_30:    lodsw
  224.     mov    ah,70h           ;attribute reverse video
  225.     stosw
  226.     loop    m_30
  227.  
  228.     mov    al,shut_cmd       ;shutdown cmd
  229.     out    status_port,al       ;get back into REAL mode 
  230. m_40:    hlt
  231.     jmp    short    m_40
  232.  
  233.     SUBTTL    Gate A20
  234.     PAGE
  235. ;--------------------------------------------------------------:
  236. ; GATE_A20                               :
  237. ; This routine controls a signal which gates address bit 20.   :
  238. ; The gate A20 signal is an output of the 8042 slave processor.:
  239. ; Address bit 20 should be gated on before entering protected  :
  240. ; mode.  It should be gated off after entering real mode from  :
  241. ; protected mode.                            :
  242. ; Input:  (AH)=0DDh addr bit 20 gated off (A20 always 0)       :
  243. ;      (AH)=0DFh addr bit 20 gated on (286 controls A20)    :
  244. ; Output: (AL)=0 operation successful.  8042 has accepted cmd  :
  245. ;      (AL)=2 Failure -- 8042 unable to accept command.     :
  246. ;--------------------------------------------------------------:
  247. gate_a20    PROC
  248.     cli             ;disable ints while using 8042
  249.     call    empty_8042   ;insure 8042 input buffer empty
  250.     jnz    gate_a20_01  ;ret if 8042 unable to accept cmd
  251.     mov    al,0D1h      ;8042 command to write output port
  252.     out    status_port,al    ;output cmd to 8042
  253.     call    empty_8042   ;wait for 8042 to accept command
  254.     jnz    gate_a20_01  ;ret if 8042 unable to accept cmd
  255.     mov    al,ah         ;8042 port data
  256.     out    port_a,al    ;output port data to 8042
  257.     call    empty_8042   ;wait for 8042 to port data
  258. gate_a20_01:
  259.     ret
  260. gate_a20    ENDP
  261. ;--------------------------------------------------------------:
  262. ; EMPTY_8042                               :
  263. ;    This routine waits for the 8042 buffer to empty        :
  264. ;    Input:    None                           :
  265. ;    Output: (AL)=0 8042 input buffer empty (ZF=1)           :
  266. ;        (AL)=2 Time out, 8042 buffer full (ZF=0)       :
  267. ;--------------------------------------------------------------:
  268. empty_8042    PROC
  269.     push    cx        ;save CX
  270.     sub    cx,cx        ;CX=0 will be time out value
  271. empty_8042_01:
  272.     in    al,status_port    ;read 8042 status port
  273.     and    al,00000010b    ;test inp. buffer full flag (D1)
  274.     loopnz    empty_8042_01    ;loop until input buffer empty 
  275.                 ; or time out
  276.     pop    cx        ;restore CX
  277.     ret
  278. empty_8042    ENDP
  279.  
  280.     SUBTTL    form_24bit_address
  281.     PAGE
  282. ;--------------------------------------------------------------:
  283. ; FORM_24BIT_ADDRESS                           :
  284. ;    Input:    DX has some segment                   :
  285. ;        CX has some offset                   :
  286. ;    Output: DX has base_lo_word                   :
  287. ;        CL has base_hi_byte                   :
  288. ;--------------------------------------------------------------:
  289. form_24bit_address    PROC
  290.     push    ax    
  291.          ;DX == s15 s14 s13 s12 s11 ... s04 s03 s02 s01 s00
  292.     rol    dx,4    
  293.          ;DX == s11 ... s04 s03 s02 s01 s00 s15 s14 s13 s12
  294.     mov    ax,dx    
  295.          ;AX == s11 ... s04 s03 s02 s01 s00 s15 s14 s13 s12
  296.     and    dl,0F0h 
  297.          ;DX == s11 ... s04 s03 s02 s01 s00   0   0   0   0
  298.     and    ax,0Fh    
  299.          ;AX ==   0 ...   0   0   0   0   0 s15 s14 s13 s12
  300.     add    dx,cx    ;form_24bit_address
  301.     mov    cx,ax    ;get base_hi_byte in CL
  302.     adc    cl,ch    ;carry in (CH=0)
  303.     pop    ax
  304.     ret
  305. form_24bit_address    ENDP
  306.  
  307.     SUBTTL    Real Mode re-entry point.
  308.     PAGE
  309.     ASSUME    ds:cseg         ; IN REAL MODE ...
  310. real:    sti                ; turn the int's on
  311.     int    20h            ; back to DOS
  312.  
  313. main        ENDP
  314.  
  315. cseg_leng    EQU    $
  316. cseg        ENDS
  317.         END    start
  318.